COMP3141 Software System Design and Implementation

COMP3141: Software System Design and Implementation

Term 2, 2023

Code and Notes (Week 2 Thursday)

Table of Contents

1 Live code

This is all the code I wrote during the practical. No guarantee that it makes any sense out of context.

module PracWeekTwo where

import Distribution.Simple.Utils
import Data.List (group, sort, sortOn)
import Data.Char (isPunctuation)
{-
  goal: 
  map f (map g xs) = map (f . g) xs

  definition of map:
  map :: (a -> b) -> [a] -> [b]
  map _ []     = []                 -- eq 1
  map f (x:xs) = f x:map f xs       -- eq 2

  proof:

  proof by structural induction on the list xs.

  case for the empty list:
  map f (map g []) = map f ([]) -- eq 1
                   = map f []
                   = []
  map (f . g) [] = [] -- eq1

     base case proven!

  inductive case:
  map f (map g xs) = map (f . g) xs -- IH

  map f (map g (x:xs)) = map f (g x : map g xs) -- eq 2
                       = f (g x) : map f (map g xs) -- eq 2
                       = f (g x) : map (f . g) xs -- IH
                       = (f . g) x : map (f . g) xs
                       = map (f . g) (x:xs)

  = side note
  -- a grammar of a basic language with probably syntax mistakes
  exp = Int x
      | Plus exp exp
      | Mult exp exp

  to prove propert P of any "exp", you need to prove the following:
  - P (Int x)
  - P e1 --> P e2 --> P (Plus e1 e2)
  - P e1 --> P e2 --> P (Mult e1 e2)

-}

-- PRACTICE QUESTIONS WEEK ONE

mySum :: Num a => [a] -> a
mySum [] = 0
mySum (x:xs) = x + mySum xs

myProduct :: Num a => [a] -> a
myProduct [] = 1
myProduct (x:xs) = x * myProduct xs

-- sum 1 + 2 + 3 + 4 + 5
-- product 1 * 2 * 3 * 4 * 5

myListBinOp :: (a -> a -> a) -> a -> [a] -> a
myListBinOp f z [] = z
myListBinOp f z (x:xs) = x `f` (myListBinOp f z xs)

-- this is how to get a type error out of the above,
-- where Num a is needed
mySum2 :: Num a => [a] -> a
mySum2 = myListBinOp (+) 0

mySum3 :: [Int] -> Int
mySum3 ns = myListBinOp (+) 0 ns

myProduct3 :: [Int] -> Int
myProduct3 ns = myListBinOp (*) 1 ns


-- foldl vs foldr
-- foldr (f) z [a,b,c] = a `f` b `f` c `f` z
-- foldr (+) z [a,b,c] = a + b + c + z
-- foldl (+) z [a,b,c] = z + c + b + a


mySum4 :: [Int] -> Int
mySum4 ns = foldr (+) 0 ns

myProduct4 :: [Int] -> Int
myProduct4 ns = foldr (*) 1 ns

{-
map (+1) [1,2,3,4]
2 : map (+1) [2,3,4]

map f [a,b,c,d]
f a : map f [b,c,d]

1 2 3 4 5


-}

-- defining map with folr
myMap :: (a -> b) -> [a] -> [b]
myMap f xs = foldr ((:) . f) [] xs

{-
  note for historians: possible errors in this comment
  [1,2,3] (-)

broken: 
myFoldL f z xs = foldr f z (reverse xs)

  foldr = 1 - (2 - 3)
  foldl = (1 - 2) - 3
  my broken fodl = 3 - (2 - 1)

-}

myFoldL :: (a -> a -> a) -> a -> [a] -> a
myFoldL f z xs = foldr (flip f) z (reverse xs)



-- word frequencies exercise

breakIntoWords :: String -> [String]
breakIntoWords = words

makeLowerCase :: String -> String
makeLowerCase = lowercase

sortStrings :: [String] -> [String]
sortStrings = sort

groupSame :: [String] -> [[String]]
groupSame = group

sortByLength :: [[String]] -> [String]
sortByLength ss = map head (reverse (sortOn length ss))

takeLongest :: Int -> [String] -> [String]
takeLongest = take

removePunctuation :: String -> String
removePunctuation s = filter (\x -> not (isPunctuation x)) s

getReport :: String -> Int -> [String]
getReport s n = takeLongest n
              $ sortByLength
              $ groupSame
              $ sortStrings
              $ map (makeLowerCase . removePunctuation)
              $ breakIntoWords s


-- fizz buzz
divides :: Integral a => a -> a -> Bool
divides a b = a `mod` b == 0

formatFB :: Int -> String
formatFB x | x `divides` 3 && x `divides` 5  = "FizzBuzz"
           | x `divides` 3  = "Fizz"
           | x `divides` 5  = "Buzz"
           | otherwise = show x

fizzBuzz :: Int -> [String]
fizzBuzz x = map formatFB [1..x]

2023-08-13 Sun 12:51

Announcements RSS